ua-parser-0.7.7.0: A library for parsing User-Agent strings, official Haskell port of ua-parser
Safe HaskellNone
LanguageHaskell2010

Web.UAParser

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

Instances details
Eq UAResult Source # 
Instance details

Defined in Web.UAParser

Data UAResult Source # 
Instance details

Defined in Web.UAParser

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 :: forall r r'. (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 # 
Instance details

Defined in Web.UAParser

Show UAResult Source # 
Instance details

Defined in Web.UAParser

Generic UAResult Source # 
Instance details

Defined in Web.UAParser

Associated Types

type Rep UAResult :: Type -> Type #

Methods

from :: UAResult -> Rep UAResult x #

to :: Rep UAResult x -> UAResult #

Serialize UAResult Source # 
Instance details

Defined in Web.UAParser

Default UAResult Source # 
Instance details

Defined in Web.UAParser

Methods

def :: UAResult #

NFData UAResult Source # 
Instance details

Defined in Web.UAParser

Methods

rnf :: UAResult -> () #

type Rep UAResult Source # 
Instance details

Defined in Web.UAParser

type Rep UAResult = D1 ('MetaData "UAResult" "Web.UAParser" "ua-parser-0.7.7.0-KWrT2VNSCvc7En7gWq2nrg" 'False) (C1 ('MetaCons "UAResult" 'PrefixI 'True) ((S1 ('MetaSel ('Just "uarFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "uarV1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "uarV2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "uarV3") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

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

Instances details
Eq OSResult Source # 
Instance details

Defined in Web.UAParser

Data OSResult Source # 
Instance details

Defined in Web.UAParser

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 :: forall r r'. (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 # 
Instance details

Defined in Web.UAParser

Show OSResult Source # 
Instance details

Defined in Web.UAParser

Generic OSResult Source # 
Instance details

Defined in Web.UAParser

Associated Types

type Rep OSResult :: Type -> Type #

Methods

from :: OSResult -> Rep OSResult x #

to :: Rep OSResult x -> OSResult #

Serialize OSResult Source # 
Instance details

Defined in Web.UAParser

Default OSResult Source # 
Instance details

Defined in Web.UAParser

Methods

def :: OSResult #

NFData OSResult Source # 
Instance details

Defined in Web.UAParser

Methods

rnf :: OSResult -> () #

type Rep OSResult Source # 
Instance details

Defined in Web.UAParser

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

Instances details
Eq DevResult Source # 
Instance details

Defined in Web.UAParser

Data DevResult Source # 
Instance details

Defined in Web.UAParser

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 :: forall r r'. (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 # 
Instance details

Defined in Web.UAParser

Show DevResult Source # 
Instance details

Defined in Web.UAParser

Generic DevResult Source # 
Instance details

Defined in Web.UAParser

Associated Types

type Rep DevResult :: Type -> Type #

Serialize DevResult Source # 
Instance details

Defined in Web.UAParser

Default DevResult Source # 
Instance details

Defined in Web.UAParser

Methods

def :: DevResult #

NFData DevResult Source # 
Instance details

Defined in Web.UAParser

Methods

rnf :: DevResult -> () #

type Rep DevResult Source # 
Instance details

Defined in Web.UAParser

type Rep DevResult = D1 ('MetaData "DevResult" "Web.UAParser" "ua-parser-0.7.7.0-KWrT2VNSCvc7En7gWq2nrg" 'False) (C1 ('MetaCons "DevResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "drFamily") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "drBrand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "drModel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))